home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
SGI Varsity Update 1998 August
/
SGI Varsity Update 1998 August.iso
/
docs6.4
/
relnotes
/
ftn90_fe
/
ch7.z
/
ch7
Wrap
Text File
|
1998-07-29
|
14KB
|
594 lines
- 1 -
7.2.1 MIPSpro Fortran 90 Front End Release Notes
- 2 -
7. _B_u_g__F_i_x_e_s
7.1 _B_u_g_s__F_i_x_e_d__i_n__M_I_P_S_p_r_o__7_._2_._1
This chapter briefly describes the bugs that
have been fixed in MIPSpro 7.2.1 F90 since
release 7.2. Some of the headings are followed
by a Silicon Graphics incident report number.
+o A bug that can arise only in the presence
of Fortran-90 internal procedures and
equivalences between variables, under the
following conditions:
+o There exist two variables equivalenced
to each other, and
+o an internal procedure refers to
exactly one of the two, and
+o the containing procedure refers only
to the other one.
Under those conditions, the 7.2MR compiler
without the patch may optimize the code for
the containing procedure as if a call to
the internal procedure could not read or
write the equivalenced variables, when in
fact it can. Here is an example program
demonstrating the failure (taken from the
bug report):
- 3 -
program test4
integer i,k
equivalence (i,k)
i = 1
call s
if (i .eq. 5) then
print *, 'pass'
call exit (0)
else
print *, 'fail', i
call exit (1)
endif
contains
subroutine s
k = 5
end subroutine s
end program test4
For this example program, the failure
occurred only at the -O3 optimization
level, but in principle it could arise at
-O2 as well. (Bug #524653) This has been
fixed.
+o -O3 and/or -pfa fail in a few cases where
nested f90 procedures refer to local arrays
from the parent procedure. This has been
fixed. (Bug #524677)
+o Wrong answers -O2 with F90 ptrs & common.
This has been fixed. (Bug #537859)
The following test case would produce
incorrect results at runtime when compiled
at optimization level -O2 and higher.
- 4 -
PROGRAM MAIN
interface
SUBROUTINE SUB1( OVER1 )
!USE TYPES
INTEGER, POINTER:: OVER1
end SUBROUTINE SUB1
end interface
!USE TYPES
INTEGER ,TARGET :: INT2
COMMON /WHATEVER/ INT2
!
INTEGER, POINTER :: OVER1
INT2 = -7
OVER1 => INT2
CALL SUB1( OVER1)
end PROGRAM MAIN
!***********************************************************************
SUBROUTINE SUB1( OVER1 )
!USE TYPES
INTEGER, POINTER:: OVER1
INTEGER ,TARGET :: INT2
COMMON /WHATEVER/ INT2
!
! Should be able to change INT2 using the OVER2%UNDER1 pointer
OVER1 = 123
IEXPECT = 123
IF( INT2 .NE. IEXPECT ) THEN
WRITE(6, '(" Test case 1.13 int pointer failed, expected ",I10, ",&
& got ", I10 )' ) IEXPECT,int2
ENDIF
print *,'done'
end subroutine SUB1
This has been fixed.
+o Code that contains internal procedures may
not be generated correctly when the -IPA or
-INLINE flags are used. Under certain
circumstances, internal compiler errors may
be generated. (Bug 511830). This has been
fixed, but the code generated, while
correct, may not be optimal.
+o Bad I/O with INTEGER(1) items in a derived
type
- 5 -
Bad output was generated when doing I/O on
arrays of derived type with integer(1) and
integer(2) elements in them. For example:
%cat iob1.f90
PROGRAM test
INTEGER :: i
INTEGER, PARAMETER :: numElements = 4
TYPE mytype
INTEGER (KIND=1) :: i1
END TYPE mytype
TYPE(mytype) :: arr(numElements)
arr(1) = mytype(1)
arr(2) = mytype(3)
arr(3) = mytype(5)
arr(4) = mytype(7)
print *,arr
END PROGRAM test
%f90 iob1.f90
%a.out
1, -1, -1, -1
Correct Output is:
1, 3, 5, 7
This has been fixed (Bug #523046)
+o The following program would abort when
compiled with 7.2 as follows:
- 6 -
%cat x.f90
program test
i = 1
j = 2
1030 format(1x,l2)
write(6,1030)i.ne.j
write(6,1030) .not. i.ne.j
%f90 x.f90
%a.out
T
lib-4171 : UNRECOVERABLE library error
An output list item is incompatible with its data edit-descriptor.
Encountered during a sequential formatted WRITE to unit 6
Fortran unit 6 is connected to a sequential formatted text file
(standard output).
Current format: 1030 FORMAT(1x,l2)
^
IOT Trap
Abort (core dumped)
This has been fixed (Bug #526202).
+o F90 printing wrong values for derived type
containing char
The following test program would print
wrong values when compiled with 7.2:
- 7 -
%cat x.f90
integer ::i
integer, parameter :: numelements = 4
type struct6
character*3::c1
end type struct6
type(struct6) :: arr6(numelements)
arr6(1)%c1 = 'abc'
arr6(2)%c1 = 'def'
arr6(3)%c1 = 'ghi'
arr6(4)%c1 = 'jkl'
print *,arr6
end
%f90 x.f90
abcbcdcdedef
Correct is: abcdefghijkl
This has been fixed (Bug #526541)
+o When the CSIN intrinsic function is used as
a dummy argument, and the -r8 or -default64
switch is specified, the compiler generates
an incorrect library entry point. At link
time, the symbol x_sin_ will be undefined.
This has been fixed. (Bug #707605).
7.2 _B_u_g_s__F_i_x_e_d__i_n__M_I_P_S_p_r_o__7_._2
This chapter briefly describes the bugs that
have been fixed in MIPSpro 7.2 F90 in the
compiler since release 7.1. Some of the
headings are followed by a Silicon Graphics
incident report number.
+o Rejecting -p flag
The following code would core dump when
compiled with -p.
a = 1.0
b = 2.0
c = matmul(a,b)
print *, c
stop
end
As -p is no longer supported; the user
should use ssrun -pcsamp, etc. to do pc-
- 8 -
sampling. The compiler was changed to
reject -p with a warning. (Bug #444089)
+o f90 fails: CVTEXPR-operation_type=72 should
not reach IL conversion
Under certain circumstances the 7.1 version
of f90 would abort with the following
error:
CVTEXPR-operation_type=72 should not reach IL conversion.
### fatal error Internal Error : unexpected type_of_operation
### Internal Error : unexpected type_of_operation
*** while processing routine VIZ_GET_SET_STATS
*** while processing routine VIZ_GET_SET_STATS
This has been fixed. (Bug #455088)
+o Internal Error : unexpected
type_of_operation with Cray directive
Use of Cay style directives (even if
commented out) causes the compiler to
abort. This has been fixed. (Bug #455685)
+o ### Null ST in Make_ID_ND
Under certain circumstances, the f90
compiler would abort with the following
error:
### Compiler Error (user routine 'transport_') during Front End Driver phase:
### Null ST in Make_ID_ND
Signal: SIGSEGV in Front End Driver phase.
This has been fixed. (Bug #456246)
+o Internal Error: Not yet translated
Under certain circumstances, the f90
compiler would abort with the following
error:
- 9 -
### fatal error Internal Error : Not yet translated
### Internal Error : Not yet translated
This has been fixed. (Bug #460856)
+o f90 compilation fails on transfer() with
CHARACTER(*) source
This has been fixed. (Bug #479806)
+o Internal Error : predecessors
Under certain circumstances, the f90
compiler would abort with the following
error:
### fatal error Internal Error : predecessors
### Internal Error : predecessors
This has been fixed. (Bug #495858)
+o -freeform with comments hang fef90
Under certain circumstances if use of
-freeform in f90 compilations would cause
the compilation to hang. This has been
fixed. (Bug #512153)